home *** CD-ROM | disk | FTP | other *** search
/ CU Amiga Super CD-ROM 24 / CU Amiga Magazine's Super CD-ROM 24 (1998)(EMAP Images)(GB)(Track 1 of 2)[!][issue 1998-07].iso / CUCD / Programming / SWI / source / man / plindex.pl < prev    next >
Encoding:
Text File  |  1997-10-17  |  12.3 KB  |  677 lines

  1. /*  $Id: plindex.pl,v 1.4 1997/10/17 16:35:32 jan Exp $
  2.  
  3.     Copyright (c) 1990 Jan Wielemaker. All rights reserved.
  4.     jan@swi.psy.uva.nl
  5.  
  6.     Purpose: Index online manual
  7.     Last Modified: 11 Octover 1995:
  8.         Updated for character_escapes handling
  9. */
  10.  
  11. :- module(online,
  12.     [ online_index/2
  13.     , online_index/0
  14.     ]).
  15.  
  16. :- set_feature(character_escapes, true).
  17.  
  18. :- asserta((user:portray(X) :-
  19.            nonvar(X),
  20.             is_list(X),
  21.             checklist(is_ascii, X), !,
  22.             format('"~s"', [X]))).
  23.     
  24. :- dynamic
  25.     last_chapter/1.
  26.  
  27. /* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
  28. This library module creates the index file for the  online  manual.   By
  29. default, as expected by help.pl, the manual is called MANUAL and resides
  30. in the Prolog library directory.  online_index[0,2] parses this file and
  31. creates the index file help_index.pl.  Toplevel:
  32.  
  33. online_index/0
  34.     Equivalent to online_index($MANUAL, $INDEX).  The two variables
  35.     are taken from the Unix environment.
  36.  
  37. online_index(+Manual, +Index)
  38.     Create index for `Manual' and write the output on `Index'.
  39.  
  40. SEE ALSO
  41.  
  42.       - The program `online' in the manual source directory
  43.       - help.pl which implements the online manual on top of this.
  44. - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
  45.  
  46. :- dynamic
  47.     page/2,
  48.     predicate/5,
  49.     function/3,
  50.     section/4,
  51.     summary/3,
  52.     end_offset/1.
  53.  
  54. online_index :-
  55.     online_index('$MANUAL', '$INDEX').
  56.  
  57. online_index(In, Out) :-
  58.     parse_summaries('summary.doc'),
  59.     open(In, read, in),
  60.     read_index,
  61.     close(in),
  62.     open(Out, write, out),
  63.     write_manual,
  64.     close(out).
  65.  
  66. %    write_manual
  67. %    Write the index file (using the asserted data) to stream `out'.
  68.  
  69. write_manual :-
  70.     format(out, '/*  $Id', []),
  71.     format(out, '$~n~n', []),
  72.     format(out, '    Generated by online_index/0~n~n', []),
  73.     format(out, '    Purpose: Index to file online_manual~n', []),
  74.     format(out, '*/~n~n', []),
  75.     format(out, ':- module(help_index,~n', []),
  76.     format(out, '    [ predicate/5~n', []),
  77.     format(out, '    , section/4~n', []),
  78.     format(out, '    , function/3~n', []),
  79.     format(out, '    ]).~n~n', []),
  80.     list(predicate, 5),
  81.     list(section, 4),
  82.     list(function, 3).
  83.  
  84. list(Name, Arity) :-
  85.     functor(Head, Name, Arity),
  86.     format(out, '%   Predicate ~w/~w~n~n', [Name, Arity]),
  87.     Head,
  88.         format(out, '~q.~n', Head),
  89.     fail.
  90. list(_, _) :-
  91.     format(out, '~n~n', []).
  92.  
  93. %    read_index/0
  94. %    Create an index in the prolog database.  Input is read from stream
  95. %    `in'
  96.  
  97. read_index :-
  98.     flag(last, _, false),
  99.     repeat,
  100.         (   flag(last, true, true)
  101.         ->    character_count(in, EndOffset),
  102.         End is EndOffset - 1,
  103.         assert(end_offset(End)), !
  104.         ;   character_count(in, Offset),
  105.         read_page(Page),
  106.         character_count(in, EndOffset),
  107.         End is EndOffset - 1,
  108.             identify_page(Offset, End, Page),
  109.             fail
  110.         ),
  111.     update_offsets.
  112.  
  113. %    read_page(-Page)
  114. %    Read the next page from stream `in'.  Pages are separeted (by
  115. %    dvi2tty) by ^L.  The last page is ended by the end-of-file. 
  116.  
  117. read_page([C|R]) :-
  118.     get0(in, C),
  119.     (   C == -1
  120.     ->  flag(last, _, true),
  121.         fail
  122.     ;   C \== 12
  123.     ), !,
  124.     read_page(R).
  125. read_page([]).
  126.     
  127. %    identify_page(+StartOffset, +EndOffset, +Page)
  128. %    Parse the start of `Page' and record it in the database as a
  129. %    page describing a certain type of data as well as were it starts
  130. %    and ends.
  131.  
  132. identify_page(Offset, EndOffset, Page) :-
  133.     parse(page(Type, TextOffset), Page, _),
  134. %    format('~w~n', page(Type, offsets(Offset, EndOffset, TextOffset))),
  135.     assert(page(Type, offsets(Offset, EndOffset, TextOffset))).
  136.  
  137. parse(page(Type, Offset)) -->
  138.     skip_blank_lines(0, Offset),
  139.     get_line(Line),
  140.     { phrase(type(Type), Line)
  141.     }.
  142.  
  143. skip_blank_lines(Sofar, Offset) -->
  144.     blank_line(Line), !,
  145.     {   length(Line, L),
  146.         NextSofar is Sofar + L
  147.     },
  148.     skip_blank_lines(NextSofar, Offset).
  149. skip_blank_lines(Offset, Offset) -->
  150.     { true }.
  151.  
  152. blank_line([10]) -->
  153.     char(10), !.
  154. blank_line([C|R]) -->
  155.     blank(C), !,
  156.     blank_line(R).
  157.  
  158. get_line([]) -->
  159.     char(10), !.
  160. get_line([C|R]) -->
  161.     [0'_, 8, C], !,
  162.     get_line(R).
  163. get_line([C|R]) -->
  164.     [C, 8, 0'_], !,
  165.     get_line(R).
  166. get_line(L) -->
  167.     [8,_], !,
  168.     get_line(L).
  169. get_line([C|R]) -->
  170.     char(C),
  171.     get_line(R).
  172.  
  173. %    Typing on the first line
  174.  
  175. type(predicate(Name, Arity, Summary)) -->
  176.     predicate_line(Name, Arity),
  177.     end_of_input, !,
  178.     { (   summary(Name, Arity, Summary)
  179.       ->  true
  180.       ;   format('ERROR: No summary for ~w/~w~n', [Name, Arity]),
  181.           Summary = ''
  182.       )
  183.         }, !.
  184. type(section([0], 'Title Page')) -->
  185.     skip_blanks,
  186.     "University of Amsterdam", !.
  187. type(section([N], 'Bibliography')) -->
  188.     skip_blanks,
  189.     "Bibliography", !,
  190.     { last_chapter([P]),
  191.       N is P + 1
  192.     }.
  193. type(section(Index, Name)) -->
  194.     section_line(Index, Name), !.
  195. type(section(Index, Name)) -->
  196.     chapter_line(Index, Name), !.
  197. type(function(Name)) -->
  198.     function_line(Name), !.
  199. type(unknown) -->
  200.     skipall(Line),
  201.     { % trace,
  202.           format('Unidentified: ~s~n', [Line])
  203.     }.
  204. type(_, _) -->
  205.     { fail }.
  206.  
  207. end_of_input([], []).
  208. skipall(Line, Line, []).
  209.  
  210. %    Identify line as describing a predicate
  211.  
  212. predicate_line(Name, Arity) -->
  213.     optional_directive,
  214.     atom(Name),
  215.     arguments(Arity), !,
  216.     {   (   functor(T, Name, Arity),
  217.         user:current_predicate(_, T)
  218.         ;   current_arithmetic_function(T)
  219.         )
  220.     ->  true
  221.     ;   format('Not a defined predicate: ~w/~w~n', [Name, Arity])
  222.     }.
  223. predicate_line(Name, 1) -->            % prefix operator
  224.     atom(Name),
  225.     skip_blanks,
  226.     predarg,
  227.     optional_dots, !.
  228. predicate_line(Name, 2) -->            % infix operator
  229.     skip_blanks,
  230.     predarg,
  231.     skip_blanks,
  232.     atom(Name),
  233.     skip_blanks,
  234.     predarg,
  235.     skipall(_), !.
  236. predicate_line(Name, 2) -->            % infix operator
  237.     skip_blanks,
  238.     predarg,
  239.     skip_blanks,
  240.     atom(Name),
  241.     skip_blanks,
  242.     predarg,
  243.     skip_blanks,
  244.     ";",
  245.     skip_blanks,
  246.     predarg,
  247.     skip_blanks.
  248. predicate_line(Name, 0) -->
  249.     atom(Name).
  250.  
  251. optional_directive -->
  252.     starts(":- "), !,
  253.     skip_blanks.
  254. optional_directive -->
  255.     { true }.
  256.  
  257. atom(Name) -->
  258.     lower_case(C1), !,
  259.     alphas(Cs),
  260.     { name(Name, [C1|Cs]) }.
  261. atom(Name) -->
  262.     symbol(C1), !,
  263.     symbols(Cs),
  264.     { name(Name, [C1|Cs]) }.
  265. atom(Name) -->
  266.     single(S), !,
  267.     { name(Name, [S]) }.
  268. atom('|') -->
  269.     "_".                % tex --> text conversion bug
  270.  
  271. alphas([C|R]) -->
  272.     alpha(C), !,
  273.     alphas(R).
  274. alphas([]) -->
  275.     { true }.
  276.  
  277. arguments(Args) -->
  278.     char(0'(),
  279.     args(Args),
  280.     char(0')).
  281.  
  282. args(Args) -->
  283.     skip_blanks,
  284.     predarg(A),
  285.     optional(0',),
  286.     args(Args0),
  287.     {sum_args(Args0, A, Args)}.
  288. args(0) -->
  289.     [].
  290.  
  291. sum_args(N, M, Sum) :-
  292.     integer(N),
  293.     integer(M), !,
  294.     Sum is N + M.
  295. sum_args(_, _, _).
  296.  
  297. optional_dots -->
  298.     skip_blanks,
  299.     starts(", ..."),
  300.     skip_blanks.
  301. optional_dots -->
  302.     { true }.
  303.  
  304. predarg -->
  305.     predarg(_).
  306.  
  307. predarg(1) -->
  308.     input_output,
  309.     alphas(_),
  310.     optional(0'/),
  311.     optional_input_output,
  312.     alphas(_), !.
  313. predarg(_) -->
  314.     "...", !.
  315. predarg(1) -->
  316.     starts("[]").
  317.  
  318. input_output -->
  319.     char(C),
  320.     { memberchk(C, "+-?:") }.
  321.  
  322. optional_input_output -->
  323.     input_output, !.
  324. optional_input_output -->
  325.     { true }.
  326.  
  327. %    Identify line as describing a function
  328.  
  329. function_line(Name) -->
  330.     function_type,
  331.     function_name(Name),
  332.     "(",
  333.     skipall(_).
  334.  
  335. function_type -->
  336.     "void (*)()", !,
  337.     skip_blanks.
  338. function_type -->
  339.     "const", !,
  340.     skip_blanks,
  341.     function_type.
  342. function_type -->
  343.     skip_blanks,
  344.     (   alpha(_),
  345.         alpha(_)
  346.     ;   "PL_"
  347.     ),
  348.     atom(_),
  349.     skip_blanks,
  350.     optional(0'(),
  351.     optional(0'*),
  352.     skip_blanks.
  353.  
  354. function_name(Name) -->
  355.     "PL_",
  356.     atom(Rest),
  357.     { concat('PL_', Rest, Name) }.
  358.  
  359. %    Identify line as starting a section
  360.  
  361. section_line(Index, Name, Line, []) :-
  362.     phrase(section_index(Index), Line, S),
  363.     name(Name, S).
  364.  
  365. section_index([C|R]) -->
  366.     skip_blanks,
  367.     number(C),
  368.     subindex(R),
  369.     skip_blanks.
  370.  
  371. subindex([S|R]) -->
  372.     char(0'.), !,
  373.     number(S),
  374.     subindex(R).
  375. subindex([]) -->
  376.     { true }.
  377.  
  378. number(N) -->
  379.     digits(D),
  380.     { D = [_|_] },
  381.     { name(N, D) }.
  382.  
  383. digits([D|R]) -->
  384.     digit(D), !,
  385.     digits(R).
  386. digits([]) -->
  387.     { true }.
  388.  
  389. %    Identify line as starting a chapter
  390.  
  391. chapter_line(Index, Name, Line, []) :-
  392.     phrase(chapter_index(Index), Line, S),
  393.     retractall(last_chapter(_)),
  394.     asserta(last_chapter(Index)),
  395.     name(Name, S).
  396.  
  397. chapter_index([Index]) -->
  398.     "Chapter",
  399.     skip_blanks,
  400.     number(Index),
  401.     ".",
  402.     skip_blanks.
  403.  
  404. starts([]) -->
  405.     !.
  406. starts([C|R]) -->
  407.     char(C),
  408.     starts(R).
  409.  
  410. %    PRIMITIVES.
  411.  
  412. skip_blanks -->
  413.     blank(_), !,
  414.     skip_blanks.
  415. skip_blanks -->
  416.     { true }.
  417.  
  418. blank(C) -->
  419.     char(C),
  420.     { blank(C) }.
  421.     
  422. blank(9).
  423. blank(32).
  424.  
  425. optional(List, In, Out) :-
  426.     is_list(List), !,
  427.     (   append(List, Out, In)
  428.     ->  true
  429.     ;   Out = In
  430.     ).
  431. optional(C) -->
  432.     char(C), !.
  433. optional(_) -->
  434.     { true }.
  435.  
  436. symbols([C|R])-->
  437.     symbol(C), !,
  438.     symbols(R).
  439. symbols([]) -->
  440.     { true }.
  441.  
  442. symbol(S) -->
  443.     char(S),
  444.     { memberchk(S, "\\#$&*+-./:<=>?@^`~") }.
  445.  
  446. single(S) -->
  447.     char(S),
  448.     { memberchk(S, "!,;|") }.
  449.  
  450. digit(D) -->
  451.     char(D),
  452.     { between(0'0, 0'9, D) }.
  453.  
  454. lower_case(C) -->
  455.     char(C),
  456.     { between(0'a, 0'z, C) }.
  457.  
  458. upper_case(C) -->
  459.     char(C),
  460.     { between(0'A, 0'Z, C) }.
  461.  
  462. alpha(C) -->
  463.     lower_case(C), !.
  464. alpha(C) -->
  465.     upper_case(C), !.
  466. alpha(C) -->
  467.     digit(C), !.
  468. alpha(0'_) -->
  469.     char(0'_).
  470.  
  471. char(C, [C|L], L).
  472.     
  473. %    update_offsets
  474.  
  475. update_offsets :-
  476.     page(section(Index, Name), offsets(F, _, O)),
  477.         (   next_index(Index, Next),
  478.         page(section(Next, _), offsets(To,_,_))
  479.         ->  true
  480.         ;    end_offset(To)
  481.         ),
  482.         From is F + O,
  483.         assert(section(Index, Name, From, To)),
  484.     fail.
  485. update_offsets :-
  486.     page(predicate(Name, Arity, Summary), offsets(F, T, O)),
  487.         From is F + O,
  488.         assert(predicate(Name, Arity, Summary, From, T)),
  489.     fail.
  490. update_offsets :-
  491.     page(function(Name), offsets(F, T, O)),
  492.         From is F + O,
  493.         assert(function(Name, From, T)),
  494.     fail.
  495. update_offsets.
  496.  
  497. %    next_index(+This, -Next)
  498. %    Return index of next section.  Note that the next of [3,4] both
  499. %    can be [3-5] and [4].
  500.  
  501. next_index(L, N) :-
  502.     (    reverse(L, [Last|Tail])
  503.     ;    reverse(L, [_,Last|Tail])
  504.     ;    reverse(L, [_,_,Last|Tail])
  505.     ;    reverse(L, [_,_,_,Last|Tail])
  506.     ),
  507.     Next is Last + 1,
  508.     reverse([Next|Tail], N).
  509.  
  510.     
  511.         /********************************
  512.         *       PARSE SUMMARIES         *
  513.         ********************************/
  514.     
  515. %    parse_summaries(+File)
  516. %    Reads the predicate summary chapter of the manual to get the
  517. %    summary descriptions.  Normally this file is called summary.doc
  518.  
  519. parse_summaries(File) :-
  520.     open(File, read, in),
  521.     parse_summaries,
  522.     close(in).
  523.  
  524. parse_summaries :-
  525.     repeat,
  526.     read_line(Line),
  527.     (   Line == end_of_file
  528.     ->  !
  529.     ;   do_summary(Line),
  530.         fail
  531.     ).
  532.  
  533. read_line(L) :-
  534.     get0(in, C),
  535.     (   C == -1
  536.     ->  L = end_of_file
  537.     ;   C == 10
  538.     ->  L = []
  539.     ;   L = [C|R],
  540.         read_line(R)
  541.     ).
  542.  
  543. do_summary(Line) :-
  544.     parse_summary(Name, Arity, Summary, Line, []), !,
  545.     (   Name == 0
  546.     ->  true
  547.     ;   assert(summary(Name, Arity, Summary))
  548.     ).
  549. do_summary(Line) :-
  550. %    trace,
  551.     format('Failed to parse "~s"~n', [Line]).
  552. do_summary(_) :- fail.
  553.  
  554. parse_summary(Name, Arity, Summary) -->
  555.     (   "\\predicatesummary"
  556.     ;   "\\functionsummary"
  557.     ),
  558.     tex_arg(Name),
  559.     tex_arg(Arity),
  560.     tex_string(Summary),
  561.     tex_comment.
  562. parse_summary(Name, Arity, Summary) -->
  563.     (   "\\oppredsummary"
  564.     ;   "\\opfuncsummary"
  565.     ),
  566.     tex_arg(Name),
  567.     tex_arg(Arity),
  568.     tex_arg(_Type),
  569.     tex_arg(_Priority),
  570.     tex_string(Summary),
  571.     tex_comment.
  572. parse_summary(0, _, _) -->
  573.     (   "%"
  574.     ;   "\\chapter"
  575.     ;   "\\section"
  576.     ;   "\\begin"
  577.     ;   "\\end"
  578.     ;   "\\newcommand"
  579.     ;   "\\pagebreak"
  580.     ;   "\\opsummary"
  581.     ), !,
  582.     string(_).
  583.  
  584. parse_summary(0, _, _) -->
  585.     [].
  586.  
  587. tex_comment -->
  588.     skip_blanks,
  589.     (   "%"
  590.     ->  string(_)
  591.     ;   []
  592.     ).
  593.  
  594. tex_arg(Value) -->
  595.     "{",
  596.     tex_arg_string(String),
  597.     "}",
  598.     { name(Value, String) }.
  599.  
  600. tex_arg_string(Value) -->
  601.     "{", !,
  602.     tex_arg_string(Sub),
  603.     "}",
  604.     tex_arg_string(Tail),
  605.     {flatten(["{", Sub, "}", Tail], Value)}.
  606. tex_arg_string([]) -->
  607.     peek(0'}), !.
  608. tex_arg_string([C|T]) -->
  609.     [C],
  610.     tex_arg_string(T).
  611.  
  612. tex_args([A|T]) -->
  613.     "{", !,
  614.     tex_arg_string(A),
  615.     "}",
  616.     tex_args(T).
  617. tex_args([]) -->
  618.     [].
  619.  
  620. tex_string(S) -->
  621.     "{",
  622.     tex_arg_string(S0),
  623.     "}",
  624.     { untex(S0, S1),
  625.       atom_chars(S, S1)
  626.     }.
  627.  
  628.  
  629. untex(In, Out) :-
  630.     phrase(untex(Out), In).
  631.  
  632. tex_expand(pllib(Lib), Out) :- !,
  633.     flatten(["library(", Lib, ")"], Out).
  634. tex_expand(predref(Name, Arity), Out) :- !,
  635.     flatten([Name, "/", Arity], Out).
  636. tex_expand(hook(Module), Out) :- !,
  637.     flatten(["Hook (", Module, ")"], Out).
  638. tex_expand(In, "") :-
  639.     format('ERROR: could not expand TeX command ~w~n', [In]).
  640.  
  641. untex(S) -->
  642.     "\\", !,
  643.     tex_command(Cmd),
  644.     tex_args(Args),
  645.     { TexTerm =.. [Cmd|Args],
  646.       tex_expand(TexTerm, S0)},
  647.     untex(S1),
  648.     { append(S0, S1, S)
  649.     }.
  650. untex([H|T]) -->
  651.     [H], !,
  652.     untex(T).
  653. untex([]) -->
  654.     [].
  655.  
  656. tex_command(Cmd) -->
  657.     tex_command_chars(Chars),
  658.     { atom_chars(Cmd, Chars) }.
  659.  
  660. tex_command_chars([C|T]) -->
  661.     letter(C), !,
  662.     tex_command_chars(T).
  663. tex_command_chars([]) -->
  664.     [].
  665.  
  666. letter(C) -->
  667.     [C],
  668.     { between(0'a, 0'z, C) }.
  669.  
  670. string("") -->
  671.     { true }.
  672. string([C|R]) -->
  673.     [C],
  674.     string(R).
  675.  
  676. peek(C, [C|T], [C|T]).
  677.